home *** CD-ROM | disk | FTP | other *** search
/ Libris Britannia 4 / science library(b).zip / science library(b) / INFO / DOSTIPS4.ZIP / DOSKYBD.TXT < prev    next >
Text File  |  1986-06-28  |  11KB  |  256 lines

  1.               IBM Advanced Function Key Techniques
  2.    (COMPUTE! Magazine January 1986 by Peter F. Nicholson, Jr.)
  3.  
  4.      Anyone who has ever redefined the function keys in an IBM BASIC
  5. program probably has wondered why there's no command to restore the
  6. keys' original definitions when the program ends.  Usually you end up
  7. disabling them or redefining them again to their default values.  But
  8. there is an alternative, and the secret lies within something called
  9. the soft key buffer.  Locating and examining this buffer can yield
  10. some interesting results.
  11.      Finding the buffer is easy if you have an IBM PC, XT or PCjr.
  12. It starts at memory location 1619 in the default memory segment.  But
  13. this is not necessarily true if you have an IBM-compatible computer.
  14. Therefore, if you're using a compatible, you should run Program 1.
  15. This program attempts to locate the soft key buffer for you.  When you
  16. find it, you should alter the buffer address (1619) in the IBM programs
  17. before running them on your compatible.  The lines where this address
  18. can be found are indicated in REMark statements within each program.
  19.      The soft key buffer is just a section of memory which stores the
  20. definitions for the function keys.  When a key is assigned a different
  21. function, its definition within the buffer is altered. A key definition
  22. can contain up to 15 characters.  If you PEEK into the buffer's memory
  23. locations, you may be surprised to find that each key is assigned not
  24. 15, but 16 positions.  Knowing the number of positions allotted for
  25. each function key makes it easy to save the buffer's contents, and
  26. therefore to preserve the keys' definitions.
  27.      Program 2 does this by reading the contents of the buffer into an
  28. array.  Then it assigns new functions to the keys.  Finally, the
  29. program lets you restore the original functions by POKEing the contents
  30. of the array back into the soft key buffer.  You can use this technique
  31. in your own programs to restore the function keys.
  32.      If you're wondering why each key is assigned 16 positions in the
  33. buffer when its definition can be only 15 characters long, disabling
  34. the keys will provide the answer.  If you PEEK at the 16 positions
  35. reserved for F1 (originally defined as LIST) and print out the ASCII
  36. values, this is what you'll see:  L I S T 0 0 0 0 0 0 0 0 0 0 0 0
  37. When you disable F1, the buffer is:  0 I S T 0 0 0 0 0 0 0 0 0 0 0 0
  38.      This seems to indicate that BASIC marks the end of a function key
  39. definition with a zero.  To prove this, run Program 3.  It demonstrates
  40. that you can restore the function keys after disabling them by merely
  41. saving the first character of each key definition (assuming, of course,
  42. that the keys have been disabled by overwriting only the first
  43. character of the definition).  That's why Program 3 needs to save only
  44. 10 bytes instead of the 160 bytes saved by Program 2.
  45.      Knowing that you can restore the disabled function keys by saving
  46. only the first character of each definition may be interesting, but
  47. the difference between 10 and 160 bytes probably is of little concern.
  48. The real power in this knowledge is that you can extend the number of
  49. characters available for a function key's definition by altering the
  50. 16th position in the buffer for that key.  This lets you assign a
  51. longer definition to a function key (at the expense of the following
  52. key, however).
  53.      For instance, you may prefer to edit programs in SCREEN 0,0,0 and
  54. WIDTH 80.  Using Program 4, you can set F9 to execute these commands
  55. even though they exceed 15 characters.  F10 becomes useless, since the
  56. size of the soft key buffer hasn't been increased -- just the length
  57. of F9's definition within that buffer.
  58.      Program 4 also lets you save the new function key definitions as
  59. a file which can be BLOADed from another program.  If you try this,
  60. don't omit the buffer address (1619) when BLOADing the file, since
  61. there is no way to insure that BASIC's segment will be the same as
  62. when you originally created the file.
  63.  
  64. Program 1:  Buffer Finder for Compatibles
  65.  
  66. 100 DEF SEG:SCREEN 0:WIDTH 80:X=0
  67. 110 CLS:PRINT "MEMORY LOCATION ";:LOCATE ,20
  68. 120 KEY 1,"LIST":A=ASC("L")
  69. 130 IF PEEK(X)=A THEN GOSUB 150 ELSE PRINT X;:LOCATE 1,20
  70. 140 X=X+1:GOTO 130
  71. 150 IF CHR$(PEEK(X+1))<>"I" THEN RETURN
  72. 160 IF CHR$(PEEK(X+2))<>"S" THEN RETURN
  73. 170 IF CHR$(PEEK(X+3))<>"T" THEN RETURN
  74. 180 CLS:PRINT "MEMORY LOCATION ";X
  75. 190 FOR J=1 TO 10:PRINT "F";J;:FOR K=0 TO 15
  76. 200 IF PEEK(X+16*(J-1)+K)>0 THEN PRINT CHR$(PEEK(X+16*(J-1)+K)); ELSE 220
  77. 210 NEXT K
  78. 220 PRINT:NEXT J
  79. 230 BEEP:INPUT "IS THIS IT ";Q$
  80. 240 IF Q$="Y" OR Q$="y" THEN END ELSE X=X+1:CLS:GOTO 110
  81.  
  82. Program 2: Restoring Function Definitions
  83.  
  84. 90 'Lines which use 1619 offset are 140 and 250
  85. 100 SCREEN 0:WIDTH 80:CLS:DEF SEG:OPTION BASE 1
  86. 110 KEY ON:DIM K$(10):FOR X=1 TO 10:K$(X)=STRING$(16,0):NEXT X
  87. 120 'Save function keys
  88. 130 FOR X=1 TO 10:FOR J=0 TO 15
  89. 140 MID$(K$(X),J+1,1)=CHR$(PEEK(1619+16*(X-1)+J))
  90. 150 NEXT J,X
  91. 160 'Redefine function keys with letters (example follows)
  92. 170 FOR X=1 TO 10:KEY X,CHR$(X+64):NEXT X:KEY LIST
  93. 180 PRINT "Function keys are redefined":PRINT "Press any key to restore"
  94. 190 KB$=INKEY$:IF KB$="" THEN 190
  95. 200 'Restore function keys
  96. 210 FOR X=1 TO 10
  97. 220 KEY X,K$(X)
  98. 230 NEXT X:CLS
  99. 240 FOR X=1 TO 10
  100. 250 J=ASC(MID$(K$(X),16,1)):IF J>0 THEN POKE 1619+16*(X-1)+15,J
  101. 260 NEXT X:CLS
  102. 260 KEY LIST
  103.  
  104. Program 3: Restoring Function Definitions
  105.  
  106. 90 'Lines which use 1619 offset are 140 and 220
  107. 100 SCREEN 0:WIDTH 80:CLS:DEF SEG
  108. 110 KEY ON:K$=STRING$(10,0)  'Storage area for function keys
  109. 120 'Save function keys
  110. 130 FOR X=1 TO 10
  111. 140 MID$(K$,X,1)=CHR$(PEEK(1619+16*(X-1)))
  112. 150 NEXT X
  113. 160 'Disable function keys
  114. 170 FOR X=1 TO 10:KEY X,"":NEXT X:KEY LIST
  115. 180 PRINT "Function keys are disabled":PRINT "Press any key to restore"
  116. 190 KB$=INKEY$:IF KB$="" THEN 190
  117. 200 'Restore function keys
  118. 210 FOR X=1 TO 10
  119. 220 POKE 1619+16*(X-1),ASC(MID$(K$,X,1))
  120. 230 NEXT X:CLS
  121. 240 KEY LIST
  122.  
  123. Program 4: Extending Definitions
  124.  
  125. 90 'Lines which use 1619 offset are 180, 290, 390, 440, 470
  126. 100 DEF SEG:STK$=STRING$(128,0):SCR$=STRING$(37,0:RESTORE 110:FOR X=1
  127.     TO 37:READ J:MID$(SCR$,X,1)=CHR$(J):NEXT X:SCR!=PEEK(VARPTR(SCR$)
  128.     +1)+256*PEEK(VARPTR(SCR$)+2)
  129. 110 DATA 85,137,229,139,118,6,41,192,138,4,139,116,1
  130. 120 DATA 1,240,137,196,184,0,6,187,0,7,185,0,2
  131. 130 DATA 186,80,24,85,205,16,92,93,202,2,0
  132. 140 SCREEN 0:WIDTH 80:CLS
  133. 150 T$="Function Key Definition"
  134. 160 LOCATE 2,(40-.5*LEN(T$)):PRINT T$
  135. 170 PRINT:PRINT
  136. 180 X=1:J=1:K=1619
  137. 190 K$=STRING$(160,0):KN$=STRING$(160,0):K=K-1
  138. 200 L=PEEK(J+K)
  139. 210 WHILE L<>0
  140. 220 MID$(K$,J,1)=CHR$(L)
  141. 230 J=J+1:L=PEEK(J+K)
  142. 240 WEND
  143. 250 PRINT "Function Key ";X;": ";MID$(K$,1,J-1)
  144. 260 PRINT:PRINT "Enter new definition or press Enter to leave unchanged"
  145. 270 LINE INPUT Q$:IF LEN(Q$)>0 THEN GOSUB 300:IF ER=1 THEN ER=0:GOTO 250
  146. 280 IF X+FIX(J/16)>9 THEN GOTO 380
  147. 290 X=X+1+FIX(J/16):K=1619+16*(X-1)-1:J=1:CALL SCR!(STK$):LOCATE 5,1:
  148.     GOTO 200
  149. 300 INPUT "Do you want a carriage return (Y/N)?;Q1$
  150. 310 IF Q1$="Y" OR Q1$="y" THEN Q$=Q$+CHR$(13)
  151. 320 IF LEN(Q$)<16 THEN J=LEN(Q$):KEY X,Q$:RETURN
  152. 330 M=1:N=16*(X-1)+1:IF N+LEN(Q$)>160 THEN BEEP:PRINT "Too long":ER=1:
  153.     RETURN
  154. 340 MID$(KN$,N,1)=MID$(Q$,M,1)
  155. 350 M=M+1:N=1+N:IF M<=LEN(Q$) THEN 340
  156. 360 IF LEN(Q$)>J THEN J=LEN(Q$)
  157. 370 RETURN
  158. 380 FOR X=1 TO 10
  159. 390 IF ASC(MID$(KN$,16*(X-1)+1,1))>0 THEN FOR J=16*(X-1)+1TO 16*X:POKE
  160.     1619+J-1,ASC(MID$(KN$,J,1)):NEXT J
  161. 400 NEXT X:CLS:KEY LIST
  162. 410 KB$=INKEY$:IF KB$="" THEN 420 ELSE 410
  163. 420 PRINT:INPUT "Do you want to save function keys as a BLOADable
  164.     file (Y/N)?";q$
  165. 430 IF Q$="Y" OR Q$="y" THEN INPUT "Filename";F$ ELSE END
  166. 440 BSAVE F$,1619,159:PRINT
  167. 450 PRINT "To load your function key file, use these commands:"
  168. 460 PRINT:PRINT
  169. 470 PRINT "DEF SEG:BLOAD ";CHR$(34);F$;CHR$(34);",1619:CLS":END
  170.  
  171. -----------------------------------------------------------------
  172.                         Cursor Correction
  173.                 (PC World May 1986 Star-Dot-Star)
  174.  
  175.      Many programs alter the size of the cursor or remove it entirely,
  176. but most restore it when you exit in the usual way.  Abnormal exits
  177. from such programs can, however, leave you with an odd-size or non-
  178. existent cursor, and some programs simply fail to restore the cursor.
  179.      FIXCURSR.COM restores the cursor to its normal size; the routine
  180. works with both monochrome and color graphics display adapters.  The
  181. program determines which adapter is currently in use, then sends the
  182. appropriate command to that adapter.
  183.  
  184. 10 DEFINT A-Z:CLS:KEY OFF:DEF FNHEX(X$)=VAL("&h"+X$)
  185. 20 READ F$
  186. 30 LOCATE 5,1,1:PRINT "Testing for data errors ...";
  187. 40 SUM=0:READ LN:IF LN<0 THEN 80
  188. 50 READ H$:IF VAL(H$)<0 THEN 70
  189. 60 SUM=(SUM+FNHEX(H$))*2:SUM=(SUM\256)+(SUM MOD 256):GOTO 50
  190. 70 READ CKSUM$:IF SUM=FNHEX(CKSUM$) THEN 40 ELSE GOTO 170
  191. 80 RESTOER:CLS:READ F$
  192. 90 LOCATE 5,1,1:PRINT "Press any key except ESC to create ";F$;": ";
  193. 100 A$=INPUT$(1):PRINT:IF A$=CHR$(27) THEN END
  194. 110 LOCATE 6,1:PRINT "Working ...";
  195. 120 OPEN F$ AS #1 LEN=1:FIELD #1,1 AS BX$
  196. 130 READ LN:IF LN<0 THEN 160
  197. 140 READ H$:IF VAL(H$)<0 THEN READ CKSUM$:GOTO 130
  198. 150 LSET BX$=CHR$(FNHEX(H$)):PUT #1:GOTO 140
  199. 160 CLOSE:PRINT:PRINT F$;" has been created.":END
  200. 170 PRINT:PRINT "Error in DATA line";STR$(LN);". ";
  201. 180 PRINT "Check and redo.":BEEP:END
  202. 1000 DATA "a:fixcursr.com"
  203. 1010 DATA 1,b4,0f,cd,10,3c,07,74,05,b9,07,06,eb,03,b9,0c,0b,-1,0a
  204. 1020 DATA 2,b4,01,cd,10,cd,20,-1,22,-1
  205.  
  206.  
  207. -----------------------------------------------------------------
  208.                          Cursor Cleaner
  209.       (PC Magazine Vol 5 No 12 June 24, 1986 User-to-User)
  210.  
  211.      There are times when you don't want a blinking cursor on-screen.
  212. CURSOR.SCR below creates a simple NOCURSOR.COM program to turn the
  213. cursor off and an equally simple CURSOR.COM program to turn it back
  214. on.  This example takes advantage of BIOS service 1 and is strictly
  215. for color/graphics adapters.  The cursor size can easily be adjusted,
  216. but must be handled differently on color and mono systems.  The color
  217. cursor is make up of 8 lines, while its mono cousin takes up 14.  The
  218. top line of each is line 0; so the bottom color line is 7 and the
  219. lowest mono line is 13.
  220.      To use BIOS service 1, put the starting line in register CH and
  221. the stopping line into CL.  The normal color cursor start/stop is 6/7.
  222. The normal mono cursor is 12/13.  Putting a &H20 (decimal 32) into CH
  223. and 0 into CL will make the cursor vanish from the screen completely.
  224.      You can produce cursors of odd shapes by changing the 0607 value
  225. in the MOV instruction.  It's simple to experiment with different
  226. values by using the BASIC
  227.  
  228. LOCATE ,,,start,stop
  229.  
  230. statement to figure out which numbers you want, then plugging them
  231. into the MOV,0607 instruction in CURSOR.COM.
  232.      Put CURSOR.SCR (in plain ASCII) and DEBUG.COM v2.0 or later on
  233. the same disk and type:
  234.  
  235. DEBUG < CURSOR.SCR
  236.  
  237. CURSOR.SCR:
  238.  
  239. A 100
  240. MOV CX,2000
  241. MOV AH,01
  242. INT 10
  243. INT 20
  244.  
  245. N NOCURSOR.COM
  246. RCX
  247. 9
  248. W
  249. A 100
  250. MOV CX,0607
  251.  
  252. N CURSOR.COM
  253. W
  254. Q
  255.  
  256.